Yang1973 Function

private function Yang1973(flow, s, v, d, dp) result(tc)

compute sediment transport capacity using Yang (1973) approach (kg/s) limitation: Yang1973 equation can be applied for noncohesive natural beds with particle sizes between 0.062 mm and 2 mm, a specific gravity of 2.65 g/cm3, and a shape factor of 0.7

References:

Yang, C. T., Unit stream power and sediment transport, J. Hydraul. Div. Am. Soc. Civ. Eng., 98(HY10), 1805– 1826, 1972.

Yang, C. T., Incipient motion and sediment transport, J. Hydraul. Div. Am. Soc. Civ. Eng., 99(HY10), 1679– 1705, 1973.

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: flow

water discharge in channel (m3/s)

real(kind=float), intent(in) :: s

channel slope (m/m)

real(kind=float), intent(in) :: v

water flow velocity in channel (m/s)

real(kind=float), intent(in) :: d

particle size of bed material (mm)

real(kind=float), intent(in) :: dp

water depth (m)

Return Value real(kind=float)

computed transport capacity (kg/s)


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: I

terms to compute transport capacity in Yang method

real(kind=float), public :: J

terms to compute transport capacity in Yang method

real(kind=float), public :: conc

sediment concentration (mg/l)

real(kind=float), public :: kVisc = 0.000001004

kinematic viscosity of water at 20 °C(m2/s)

real(kind=float), public :: vs

channel Unit Stream Power (m/s)

real(kind=float), public :: vsCrit

critical channel Unit Stream Power (m/s)


Source Code

FUNCTION Yang1973 &
!
(flow, s, v, d, dp) &
!
RESULT (tc)

IMPLICIT NONE

!Arguments with intent in:
REAL (KIND = float), INTENT(IN) :: flow !!water discharge in channel (m3/s)
REAL (KIND = float), INTENT(IN) :: s !!channel slope (m/m)
REAL (KIND = float), INTENT(IN) :: v !!water flow velocity in channel (m/s)
REAL (KIND = float), INTENT(IN) :: d !!particle size of bed material (mm)
REAL (KIND = float), INTENT(IN) :: dp !!water depth (m)

!local declarations:
REAL (KIND = float) :: tc !!computed transport capacity (kg/s)
REAL (KIND = float) :: vs !! channel Unit Stream Power (m/s)
REAL (KIND = float) :: vsCrit !! critical channel Unit Stream Power (m/s)
REAL (KIND = float) :: kVisc = 0.000001004 !!kinematic viscosity of water at 20 °C(m2/s)
REAL (KIND = float) :: I, J !! terms to compute transport capacity in Yang method
REAL (KIND = float) :: conc !!sediment concentration (mg/l)

!------------end of declaration------------------------------------------------

!compute channel unit stream power
vs = v * s

!compute channel critical unit stream power
vsCrit = CriticalVelocity(d, dp, s) * s

!compute I and J

!I = 5.435 - 0.286 * LOG (FallVelocity(d) * (d/1000.) / kVisc) - &
I = 6.0 - 0.286 * LOG (FallVelocity(d) * (d/1000.) / kVisc) - &
    0.457 * LOG (ShearVelocity(dp,s)/FallVelocity(d)) 
    
!J = 1.799 - 0.409 * LOG (FallVelocity(d) * (d/1000.) / kVisc) - &
J = 1.5 - 0.409 * LOG (FallVelocity(d) * (d/1000.) / kVisc) - &
    0.314 * LOG (ShearVelocity(dp,s)/FallVelocity(d)) 
    
    
!if (isnan (I)) then
!  write(*,*) 'I isnan', FallVelocity(d), ShearVelocity(dp,s)
!   pause
!end if    
!
!if (isnan (J)) then
!  write(*,*) 'J isnan', FallVelocity(d), ShearVelocity(dp,s)
!   pause
!end if    
    
!compute sediment concentration (ppm or mg/l)
IF (vs > vsCrit) THEN
   conc = EXP ( I + J * LOG((vs - vsCrit)/FallVelocity(d)) )
ELSE
   conc = 0.
END IF

IF (conc < 0.) THEN
  conc = 0.
END IF

!compute transport capacity (kg/s)
tc = flow * conc / 1000.


END FUNCTION Yang1973